IrrigationConfig Subroutine

public subroutine IrrigationConfig(file, path_out, dtOut)

configure irrigation

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: file
character(len=*), intent(in) :: path_out
integer(kind=short), intent(in) :: dtOut

dt out irrigation


Variables

Type Visibility Attributes Name Initial
logical, public :: check
type(IniList), public :: iniDb
integer(kind=short), public :: k
character(len=10), public :: secNumber
character(len=300), public :: string

Source Code

SUBROUTINE IrrigationConfig &
!
(file, path_out, dtOut)

IMPLICIT NONE

!Arguments with intent (in)
CHARACTER (LEN = *), INTENT (IN) :: file
CHARACTER (LEN = *), INTENT(IN) :: path_out
INTEGER (KIND = short), INTENT(IN) :: dtOut !!dt out irrigation

!local declarations
TYPE (IniList) :: iniDb
CHARACTER (LEN = 10)   :: secNumber
INTEGER (KIND = short) :: k
CHARACTER (LEN = 300) :: string
LOGICAL :: check

!-----------------------------------end of declarations------------------------

CALL IniOpen (file, iniDB)

!read EPSG (used only for witing string into output file)
epsg = IniReadString ('epsg', iniDB)

!Allocate fields
fields % count = IniReadInt ('count', iniDB)
ALLOCATE ( fields % elem (fields % count) )

!read intake and irrigation district properties
DO k = 1, fields % count
  secNumber = ToString (k)
  fields % elem (k) % name = IniReadString ('name', iniDB, section = secNumber)
  fields % elem (k) % id = IniReadString ('id', iniDB, section = secNumber)
  string = IniReadString ('max-discharge', iniDB, section = secNumber)
  fields % elem (k) % max_discharge = SetDailyArray (string)
  fields % elem (k) % xy % northing = IniReadReal ('northing', &
                                      iniDB, section = secNumber)
  fields % elem (k) % xy % easting = IniReadReal ('easting', iniDB, &
                                     section = secNumber)
  string = IniReadString ('e-flow', iniDB, section = secNumber)
  fields % elem (k) % e_flow = SetDailyArray (string)
  fields % elem (k) % doy_start = IniReadInt ('doy-start', iniDB, &
                                  section = secNumber)
  fields % elem (k) % doy_stop = IniReadInt ('doy-stop', iniDB, &
                                 section = secNumber)
  fields % elem (k) % sat_max = IniReadReal ('sat-max', iniDB, &
                                section = secNumber)
  !read irrigation efficiency. Default = 1
  IF (KeyIsPresent ('eta', iniDB, section = secNumber)) THEN
      fields % elem (k) % eta = IniReadReal ('eta', iniDB, &
                                section = secNumber)
      IF ( fields % elem (k) % eta > 1. ) THEN
          CALL Catch ('warning', 'Irrigation',  &
          'irrigation efficiency > 1 in intake: ',  &
           argument = fields % elem (k) % name )
      END IF
      IF ( fields % elem (k) % eta < 0. ) THEN
          CALL Catch ('warning', 'Irrigation',  &
          'irrigation efficiency < 0 in intake: ',  &
           argument = fields % elem (k) % name )
      END IF
  ELSE
      fields % elem (k) % eta = 1.
  END IF
  !load i_th subbasin mask
  CALL GridByIni (iniDB, fields % elem (k) % mask, secNumber, 'mask')
  fields % elem (k) % area = GetArea (fields % elem (k) % mask)
  
  !set intake location in local grid reference system
  CALL GetIJ (fields % elem (k) % xy % easting, &
              fields % elem (k) % xy % northing, &
              mask, fields % elem (k) % r, fields % elem (k) % c, check)
        IF (.NOT. check) THEN
          CALL Catch ('error', 'Irrigation',  &
             'river intake located out of discharge grid in intake: ',  &
              argument = TRIM(fields % elem (k) % name) )
        END IF
END DO

!Open files for output

IF ( dtOut > 0 ) THEN

    !diverted discharge
    unitIrrigationDiverted = GetUnit ()
    OPEN (unit = unitIrrigationDiverted, &
          file = path_out(1:LEN_TRIM(path_out))//'irrigation_diverted.fts')

    !populate output file with metadata information
    WRITE (unitIrrigationDiverted,'(a)') 'description = irrigation discharge &
                                          diverted from water courses'
    WRITE (unitIrrigationDiverted,'(a)') 'unit = m3/s'
    WRITE (unitIrrigationDiverted,'(a)') 'epsg = ' // TRIM (epsg)
    WRITE (unitIrrigationDiverted,'(a,i)') 'count = ', fields % count
    WRITE (unitIrrigationDiverted,'(a,i)') 'dt = ', dtOut
    WRITE (unitIrrigationDiverted,'(a)') 'missing-data =   -999.900'
    WRITE (unitIrrigationDiverted,'(a)') 'offsetz =      0.000'

    !metadata section
    WRITE (unitIrrigationDiverted,*) !blank line
    WRITE (unitIrrigationDiverted,'(a)') 'metadata'

    DO k = 1, fields % count
        WRITE (unitIrrigationDiverted,'(a,3x,a,3x,3f15.3)') &
              TRIM(fields % elem (k) % name), &
              TRIM(fields % elem (k) % id), &
              fields % elem (k) % xy % easting, &
              fields % elem (k) % xy % northing, 0.00
    END DO

    !data section
    WRITE (unitIrrigationDiverted,*) !blank line
    WRITE (unitIrrigationDiverted,'(a)') 'data'
    WRITE (unitIrrigationDiverted,'(a)', advance = 'no') 'DateTime '

    DO k = 1, fields % count - 1
        WRITE (unitIrrigationDiverted,'(a, 1x)', advance = 'no') &
               TRIM (fields % elem (k) % id)
    END DO

    WRITE (unitIrrigationDiverted,'(a)') &
           TRIM ( fields % elem (fields % count) % id )


    !downstream discharge
    unitIrrigationDownstream = GetUnit ()
    OPEN (unit = unitIrrigationDownstream, &
          file = path_out(1:LEN_TRIM(path_out))//'irrigation_downstream.fts')

    !populate output file with metadata information
    WRITE (unitIrrigationDownstream,'(a)') 'description = irrigation  &
                                            discharge downstream the intake'
    WRITE (unitIrrigationDownstream,'(a)') 'unit = m3/s'
    WRITE (unitIrrigationDownstream,'(a)') 'epsg = ' // TRIM (epsg)
    WRITE (unitIrrigationDownstream,'(a,i)') 'count = ', fields % count
    WRITE (unitIrrigationDownstream,'(a,i)') 'dt = ', dtOut
    WRITE (unitIrrigationDownstream,'(a)') 'missing-data =   -999.900'
    WRITE (unitIrrigationDownstream,'(a)') 'offsetz =      0.000'

    !metadata section
    WRITE (unitIrrigationDownstream,*) !blank line
    WRITE (unitIrrigationDownstream,'(a)') 'metadata'

    DO k = 1, fields % count
        WRITE (unitIrrigationDownstream,'(a,3x,a,3x,3f15.3)') &
              TRIM(fields % elem (k) % name), &
              TRIM(fields % elem (k) % id), &
              fields % elem (k) % xy % easting, &
              fields % elem (k) % xy % northing, 0.00
    END DO

    !data section
    WRITE (unitIrrigationDownstream,*) !blank line
    WRITE (unitIrrigationDownstream,'(a)') 'data'
    WRITE (unitIrrigationDownstream,'(a)', advance = 'no') 'DateTime '

    DO k = 1, fields % count - 1
        WRITE (unitIrrigationDownstream,'(a, 1x)', advance = 'no') &
               TRIM (fields % elem (k) % id)
    END DO

    WRITE (unitIrrigationDownstream,'(a)') &
           TRIM ( fields % elem (fields % count) % id )
    
    
    !upstream discharge
    unitIrrigationUpstream = GetUnit ()
    OPEN (unit = unitIrrigationUpstream, &
          file = path_out(1:LEN_TRIM(path_out))//'irrigation_upstream.fts')

    !populate output file with metadata information
    WRITE (unitIrrigationUpstream,'(a)') 'description = irrigation  &
                                            discharge upstream the intake'
    WRITE (unitIrrigationUpstream,'(a)') 'unit = m3/s'
    WRITE (unitIrrigationUpstream,'(a)') 'epsg = ' // TRIM (epsg)
    WRITE (unitIrrigationUpstream,'(a,i)') 'count = ', fields % count
    WRITE (unitIrrigationUpstream,'(a,i)') 'dt = ', dtOut
    WRITE (unitIrrigationUpstream,'(a)') 'missing-data =   -999.900'
    WRITE (unitIrrigationUpstream,'(a)') 'offsetz =      0.000'

    !metadata section
    WRITE (unitIrrigationUpstream,*) !blank line
    WRITE (unitIrrigationUpstream,'(a)') 'metadata'

    DO k = 1, fields % count
        WRITE (unitIrrigationUpstream,'(a,3x,a,3x,3f15.3)') &
              TRIM(fields % elem (k) % name), &
              TRIM(fields % elem (k) % id), &
              fields % elem (k) % xy % easting, &
              fields % elem (k) % xy % northing, 0.00
    END DO

    !data section
    WRITE (unitIrrigationUpstream,*) !blank line
    WRITE (unitIrrigationUpstream,'(a)') 'data'
    WRITE (unitIrrigationUpstream,'(a)', advance = 'no') 'DateTime '

    DO k = 1, fields % count - 1
        WRITE (unitIrrigationUpstream,'(a, 1x)', advance = 'no') &
               TRIM (fields % elem (k) % id)
    END DO

    WRITE (unitIrrigationUpstream,'(a)') &
           TRIM ( fields % elem (fields % count) % id )

END IF

!allocate variables:
CALL NewGrid (Qirrigation, mask, 0.)
CALL NewGrid (irrigationFlux, mask, 0.)
CALL NewGrid (cpQriver, mask, 0.)


RETURN
END SUBROUTINE IrrigationConfig